ComputeSpatialAverageCanopy Subroutine

public subroutine ComputeSpatialAverageCanopy(dt, canopyStorage, throughfall, pt)

Compute spatial average of canopy interception variables

Arguments

Type IntentOptional Attributes Name
integer(kind=short), intent(in) :: dt

time step (s)

type(grid_real), intent(in) :: canopyStorage

water canopy storage (mm)

type(grid_real), intent(in) :: throughfall

effective rain reaching soil surface (m/s)

type(grid_real), intent(in) :: pt

potential transpiration from canopy (m/s)


Variables

Type Visibility Attributes Name Initial
integer(kind=short), public :: count
integer(kind=short), public :: i

Source Code

SUBROUTINE ComputeSpatialAverageCanopy   & 
!
 (dt, canopyStorage, throughfall,  pt)  

IMPLICIT NONE

!arguments with intent in:
INTEGER (KIND = short), INTENT(IN) :: dt !!time step (s) 
TYPE (grid_real), INTENT(IN) :: canopyStorage !!water canopy storage (mm)
TYPE (grid_real), INTENT(IN) :: throughfall !! effective rain reaching soil surface (m/s)
TYPE (grid_real), INTENT(IN) ::  pt!! potential transpiration from canopy (m/s)

!local declarations
INTEGER (KIND = short) :: i
INTEGER (KIND = short) :: count
!-------------------------------end of declaration-----------------------------

DO i = 1, nextents
    count = 0

    !canopy storage
    IF ( canopyout (1) ) THEN
      count = count + 1
      extents (i) % canopy (count) = &
            GetMean (canopyStorage,  maskInteger = extents (i) % mask )
    END IF
    
    !throughfall
    IF ( canopyout (2) ) THEN
      count = count + 1
      extents (i) % canopy (count) = &
            GetMean (throughfall,  maskInteger = extents (i) % mask ) * &
            dt * 1000. !conversion to mm over dt
    END IF
    
    !transpiration (evaporation from canopy)
    IF ( canopyout (3) ) THEN
      count = count + 1
      extents (i) % canopy (count) = &
            GetMean (pt,  maskInteger = extents (i) % mask ) * &
            dt * 1000. !conversion to mm over dt
    END IF
 
END DO

RETURN
END SUBROUTINE ComputeSpatialAverageCanopy